MorphologyInit Subroutine

public subroutine MorphologyInit(inifile, mask)

Initialize morphological properties

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: inifile

name of configuration file

type(grid_integer), intent(in) :: mask

domain analysis


Variables

Type Visibility Attributes Name Initial
type(grid_integer), public :: fdir

overlay of flowdirection on mask

integer(kind=short), public :: i
integer(kind=short), public :: j
real(kind=float), public :: maxReachLength

max length of a reach (m)

integer(kind=short), public :: reachFileExport

export reach list to file

integer(kind=short), public :: reachShpExport

export shape file of reach network

real(kind=float), public :: slopeCorrection

slope value to correct negative values

character(len=100), public :: string

Source Code

SUBROUTINE MorphologyInit &
!
( inifile, mask )

IMPLICIT NONE

! arguments with intent(in).
CHARACTER (LEN = *), INTENT(IN) :: inifile  !!name of configuration file
TYPE (grid_integer), INTENT(IN) :: mask !!domain analysis

! local declarations
REAL (KIND = float) :: maxReachLength  !!max length of a reach (m)
REAL (KIND = float) :: slopeCorrection !! slope value to correct negative values
TYPE (grid_integer) :: fdir !!overlay of flowdirection on mask
INTEGER (KIND = short) :: reachFileExport !!export reach list to file
INTEGER (KIND = short) :: reachShpExport !!export shape file of reach network
CHARACTER (LEN = 100) :: string
INTEGER (KIND = short) :: i,j

!-------------------------end of declarations----------------------------------

!open and load configuration file
CALL IniOpen (inifile, iniDB)

!read dem
IF (SectionIsPresent('dem', iniDB)) THEN
  CALL GridByIni (iniDB, dem, section = 'dem')
  IF  ( .NOT. CRSisEqual (mask = mask, grid = dem, checkCells = .TRUE.) ) THEN
       CALL Catch ('error', 'MorphologicalProperties',   &
			    'wrong spatial reference in digital elevation model' )
  END IF
  dem_loaded = .TRUE.
END IF

!flow direction
IF (SectionIsPresent('flow-direction', iniDB)) THEN
  CALL GridByIni (iniDB, flowDirection, section = 'flow-direction')
  !set flow direction convention
  IF (KeyIsPresent('flow-direction-convention', iniDB, section = 'flow-direction' )) THEN
     string = IniReadString ('flow-direction-convention', iniDB, section = 'flow-direction' )
     CALL SetFlowDirectionConvention (string)
  ELSE
      CALL Catch ('error', 'MorphologicalProperties',   &
			     'flow-direction-convention missing in section flow-direction ' )
  END IF
 
  IF  ( .NOT. CRSisEqual (mask = mask, grid = flowDirection, checkCells = .TRUE.) ) THEN
     CALL Catch ('error', 'MorphologicalProperties',   &
			     'wrong spatial reference in flow direction' )
  END IF
  flowDirection_loaded = .TRUE.
END IF


!flow accumulation
IF (SectionIsPresent('flow-accumulation', iniDB)) THEN
  CALL GridByIni (iniDB, flowAccumulation, section = 'flow-accumulation')
  IF  ( .NOT. CRSisEqual (mask = mask, grid = flowAccumulation, checkCells = .TRUE.) ) THEN
     CALL Catch ('error', 'MorphologicalProperties',   &
			     'wrong spatial reference in flow accumulation' )
  END IF
  flowAccumulation_loaded = .TRUE.
END IF


!stream network
IF ( SectionIsPresent ('stream-network', iniDB) ) THEN
    
   IF ( KeyIsPresent ('max-reach-length', iniDB, 'stream-network') ) THEN
       maxReachLength = IniReadReal ('max-reach-length', iniDB, 'stream-network')
   ELSE
       maxReachLength = - 1.
   ENDIF
   
   IF ( KeyIsPresent ('negative-slope-correction', iniDB, 'stream-network') ) THEN
       slopeCorrection = IniReadReal ('negative-slope-correction', iniDB, 'stream-network')
   ELSE
       slopeCorrection = - 1.
   ENDIF
   
   IF ( KeyIsPresent ('file-export', iniDB, 'stream-network') ) THEN
       reachFileExport = IniReadInt ('file-export', iniDB, 'stream-network')
   ELSE
       reachFileExport = - 1.
   ENDIF
   
   IF ( KeyIsPresent ('shp-export', iniDB, 'stream-network') ) THEN
       reachShpExport = IniReadInt ('shp-export', iniDB, 'stream-network')
   ELSE
       reachShpExport = - 1.
   ENDIF
   
   !create temporary flow direction grid 
   CALL NewGrid (fdir, mask, 0)
   
   !mask overlay
   DO i = 1, mask % idim
       DO j = 1, mask % jdim
           IF ( mask % mat (i,j) /= mask % nodata ) THEN
               fdir % mat (i,j) = flowDirection % mat (i,j)
           END IF
       END DO
   END DO
   
   
   CALL BuildReachNetwork (maxReachLength, slopeCorrection, fdir, &
                          flowAccumulation, dem, reachFileExport, &
                          reachShpExport, streamNetwork )
   
   !destroy fdir
   CALL GridDestroy (fdir)
   
   streamNetworkCreated = .TRUE.
   
END IF


!close ini
CALL IniClose (iniDB)

RETURN
END SUBROUTINE MorphologyInit